home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Languguage OS 2
/
Languguage OS II Version 10-94 (Knowledge Media)(1994).ISO
/
language
/
embedded
/
simulato
/
v2_3_mc6.tz
/
v2_3_mc6
/
testfiles
/
sim35.asm
< prev
next >
Wrap
Assembly Source File
|
1994-05-02
|
72KB
|
1,226 lines
; Class CDA 3101, Fall '91
; Assn Assembler/Simulator for SIM 35 hypothetical computer
; Progam Name sim35.asm
;
; Description: This program uses the Pseudo Assembler from programing
; assignment #2 as a basis for a full fleged assembler for the
; SIM 35 hypothetical microporcessor. It also simulates execution
; of native SIM35 code on a M68000 microprocessor. The Pseudo
; Assembler took single lines of input in assembly and checked
; their syntax and produced a valid label table. The new
; implementation of this program takes single lines of input and
; outputs errors if any syntax errors are encountered, produces a
; valid label table that includes the addresses which corespond to
; each label, and outputs "half-assembled code" to an area of
; memory in the reserved in the data block of the program. This
; 1/2 code consists of instructions in the following format:
; 1st byte :opcode in hex
; 2nd byte :register operand in hex (not ASCII), or 00
; 3rd byte :register operand in hex (not ASCII), or...
; 3rd, 4th, and subsequent bytes: label or address in ASCII
; When the END directive is encountered, then the second pass
; begins if and only if no errors were encountered in the first
; pass. The second pass assembles the half-assembled code and
; the valid label table's addresses into native sim35 code and
; stores it at $3000+ which simulates the loading address $0 in
; the sim35 computer. The last part of the program uses the
; 68000's instruction set to simulate instructions from the sim35
; code. Registers D0-D3 are used to represent the registers R0-
; R3 in the sim35 computer. Memory addresses $3000-$33FF
; simulate the sim35's 10 bit addressable space: $0-$3FF.
****************************
* *
* DATA BLOCK *
* *
****************************
;
;------------------------------------------------------------------------------
; The following two storage spaces are set asside for valid labels. The first
; (ValidLabels) holds all valid labels encountered during assembly. This is the
; list that is checked to see if a label is a duplicate. The other list holds
; all labels encountered as operands and these are checked individually against
; the ValidLabels list after the END directive is encountered. Those labels
; appearing on this list that do not also appear on the ValidLabels list are
; output as undefined label errors (see below in the data block). Each of
; these lists is delimited by null characters and terminated by a carriage
; return (ASCII $D).
;
;
org $5000
ValidLabels ds.b $168 ;12 bytes x 30 lines=$168
UndefLabels ds.b $21C ;9 bytes x 60 operands=$21C
;
;------------------------------------------------------------------------------
; The following three constants are useful in dealing with strings.
;
;
CR equ $D ;carriage return
null equ $0 ;null string
space equ $20 ;space
;
;------------------------------------------------------------------------------
; The following string constants are used in input and output formatting.
;
;
cnop 0,2 ;alligns on a word boundary
Prompt dc.b 'Enter sourcecode: ',0
cnop 0,2 ;alligns on a word boundary
Heading dc.b 'Results',0
cnop 0,2 ;alligns on a word boundary
Line dc.b '-------',0
cnop 0,2 ;alligns on a word boundary
LongLine dc.b '----------------------------------------------------------',0
;
;------------------------------------------------------------------------------
; The next few data spaces are buffers for input and manipulation of input.
;
;
cnop 0,2 ;alligns on a word boundary
Input ds.b 41 ;room for a line of input
cnop 0,2 ;alligns on a word boundary
Label ds.b 41 ;space to store label portion of input
cnop 0,2 ;alligns on a word boundary
Opcode ds.b 41 ;space to store opcode portion of input
cnop 0,2 ;alligns on a word boundary
Operands ds.b 41 ;space to store operands from input
cnop 0,2 ;alligns on a word boundary
TempLabel ds.b 41 ;place to store a label while checking it
cnop 0,2 ;alligns on a word boundary
Program ds.b $4CE ;lots 'o' space for 1/2 assembled code
cnop 0,2 ;alligns on a word boundary
Object.Ptr ds.l 1 ;ptr to final location of obj code
cnop 0,2 ;alligns on a word boundary
Prog.Ptr ds.l 1 ;ptr to addr for next line of 1/2 code
;
;------------------------------------------------------------------------------
; The following flags and indicators are basically paramters passed from the
; main body of the progam to subroutines and returned with altered values.
; The boolean flags occupy a byte each and are set to either 1 or 0 (the
; meanings of these settings are discussed as each flag is enoucountered in the
; program).
;
;
cnop 0,2 ;alligns on a word boundary
OperandType ds.b 1 ;If set to 0=RR, 1=RM, 2= none
cnop 0,2 ;alligns on a word boundary
OpcodeVal ds.b 1 ;place to store actual #val of Opcode
cnop 0,2 ;alligns on a word boundary
ValidFlag ds.b 1 ;boolean flag to show if label is valid
cnop 0,2 ;alligns on a word boundary
DupFlag ds.b 1 ;boolean flag showing label duplication
cnop 0,2 ;alligns on a word boundary
EndofProg ds.b 1 ;boolean flag representing end directive
cnop 0,2 ;alligns on a word boundary
ErrorFlag ds.b 1 ;boolean flag:0=do second pass,1=don't
cnop 0,2 ;alligns on a word boundary
NegFlag ds.b 1 ;boolean flag:sign of ds or dc operand
;
;------------------------------------------------------------------------------
; The next block of data contains strings used to alert user of errors in plain
; english. Each is terminated in a null so the given subroutines can detect the
; end of each string.
;
;
cnop 0,2
InvalidLab dc.b 'Invalid Label',0
cnop 0,2 ;alligns on a word boundary
Miss1Operand dc.b 'First Operand Missing',0
cnop 0,2 ;alligns on a word boundary
Miss2Operand dc.b 'Second Operand Missing',0
cnop 0,2 ;alligns on a word boundary
MissingOpcode dc.b 'Missing Opcode',0
cnop 0,2 ;alligns on a word boundary
IllegalOperand dc.b 'Illegal Operand',0
cnop 0,2 ;alligns on a word boundary
Inval1Oprnd dc.b 'First Operand Invalid',0
cnop 0,2 ;alligns on a word boundary
Inval2Oprnd dc.b 'Second Operand Invalid',0
cnop 0,2 ;alligns on a word boundary
InvalidOpcode dc.b 'Invalid Opcode',0
cnop 0,2 ;alligns on a word boundary
DuplicateLab dc.b 'Duplicate Label',0
cnop 0,2 ;alligns on a word boundary
CantAssem dc.b 'Error(s) encountered-Cannot Assemble',0
cnop 0,2 ;alligns on a word boundary
SecondMess dc.b 'Second pass now underway...',0
cnop 0,2 ;alligns on a word boundary
ProgRun dc.b 'Program is now running...',0
;
;------------------------------------------------------------------------------
; The undefined label error is a continuous string starting at UDLabelErr and
; continuing through UdLabelName. UdLabelName's contents are filled before
; string is written (UdLabelName's contents will be terminated with a null at
; this time). Thus the label's name is append to make a custom message.
;
;
cnop 0,2 ;alligns on a word boundary
UDLabelErr dc.b 'Undefined Label: '
UdLabelName ds.b 40
;
;------------------------------------------------------------------------------
; The entries of the following opcode table have the following format:
; mnemonic,$FE,opcode in hex, $FF. Each entry is in upper case and the opcode of
; each is used later in assembling the object code, except with the assembler
; directives END, DC, and DS, which have false opcodes used to inform the
; assembler to carry out a directive.
;
;
cnop 0,2 ;alligns on a word boundary
OpTable dc.b 'AR',$FE,0,$FF ;Add register
dc.b 'SR',$FE,1,$FF ;Subtract register
dc.b 'LR',$FE,2,$FF ;Load register
dc.b 'NLR',$FE,3,$FF ;Negate and Load register
dc.b 'MR',$FE,4,$FF ;Multiply register
dc.b 'DR',$FE,5,$FF ;Divide register
dc.b 'BC',$FE,6,$FF ;Branch Conditionally
dc.b 'A',$FE,7,$FF ;Add Memory
dc.b 'S',$FE,8,$FF ;Subtract Memory
dc.b 'L',$FE,9,$FF ;Load Memory
dc.b 'M',$FE,$A,$FF ;Multiply Memory
dc.b 'D',$FE,$B,$FF ;Divide Memory
dc.b 'ST',$FE,$C,$FF ;Store Memory
dc.b 'EXT',$FE,$D,$FF ;Exit
dc.b 'DPR',$FE,$E,$FF ;Dump Registers
dc.b 'DPM',$FE,$F,$FF ;Dump Memory
dc.b 'DC',$FE,$10,$FF ;Define Constant
dc.b 'DS',$FE,$11,$FF ;Define Storage
dc.b 'END',$FE,$12,$FF ;End Assembly
dc.b $D ;End of table marker (carriage return)
;
;------------------------------------------------------------------------------
; The following storage spaces are used by the simulation portion of this
; program.
;
;
cnop 0,2 ;alligns on a word boundary
DestReg ds.b 1 ;Temp storage for destination register
cnop 0,2 ;alligns on a word boundary
CondCode ds.b 1 ;Simulated condition code
************************************
* *
* PROGRAM SOURCECODE *
* *
************************************
;
;------------------------------------------------------------------------------
; The first segment reads a line of input. The label heading 'ReadANewLine' is
; invoked when a new line needs to be read.
;
;
org $1000
jsr ClearScreen
move.b #$FF,ValidLabels ;Valid Label list is empty
move.b #CR,UndefLabels ;Undefined Label list is empty
move.b #0,ErrorFlag ;no error encountered yet
move.l #$0000,Object.Ptr ;objective code starts at address 0
move.l #Program,Prog.Ptr ;set pointer to begining of source strg
ReadANewLine move.l #Prompt,A0 ;Points to input prompt
jsr WriteString ;Places prompt on screen
movea.l #Input,A0 ;Place to store line of input
jsr ReadString ;Read in line of input from keyboard
jsr WriteEOL ;Produce a carriage return
movea.l #Heading,A0 ;pointer to heading
jsr WriteString ;Prints heading
jsr WriteEOL ;produce a carriage return
movea.l #Line,A0 ;Pointer to a line
jsr WriteString ;Draws the line
jsr WriteEOL ;produce a carriage return
movea.l #Input,A4 ;Pointer (called Ptr from now on) to input
;
;------------------------------------------------------------------------------
; For each new line the temporary storage place for each field is
; set to empty (i.e. their first characters are end of field characters [nulls]
;
;
move.b #null,Label ;end of field marker
move.b #null,Opcode ;end of field marker
move.b #null,Operands ;end of field marker
;
;------------------------------------------------------------------------------
; The next segment of code invokes the Scan and SkipSpaces subroutines in order
; to split the Input line into three distinct fields, Label, Opcode, and
; Operands.
;
;
movea.l #Label,A5 ;Set ptr to Label temporary field
jsr Scan ;Fill Label field from Input
movea.l #Opcode,A5 ;Set ptr to Opcode temporary field
jsr SkipSpaces ;Skip ahead to next characters in string
jsr Scan ;Fill Opcode field from Input
movea.l #Operands,A5 ;Set ptr to Operands temporary field
jsr SkipSpaces ;Skip ahead to next characters in string
jsr Scan ;File Operands field from Input
;
;
;------------------------------------------------------------------------------
; The Analyize segment calls three main subroutines, ExamineLabel,
; ExamineOpcode, and ExamineOperands. These three subroutines determine
; wheter the syntax of each statement is legal, wether symbols are valid or
; duplicated, and if the number and type of operands is in agreement with the
; opcode's specifications. These subroutines also store valid labels in a
; table, output valid mnemonic's opcodes, display error messages and store
; valid symbol opcodes in a table for cross referencing with the valid labels
; table at the end of assembly.
;
;
Analyze subq #4,A7 ;pop last jsr to scan from stack
move.b #0,EndofProg ;set flag to false (not end of program)
jsr ExamineLabel ;examine syntax of Label temp. string
jsr ExamineOpcode ;examine syntax of Opcode temp. string
cmpi.b #1,(EndofProg) ;was END directive encountered?
beq EndProg ;if so, branch ahead to end
jsr ExamineOperand ;examine syntax of Operands temp. string
jsr WriteEOL ;output a carriage return
movea.l #LongLine,A0 ;points to line which seperates input
jsr WriteString ;draws this dividing line
jsr WriteEOL ;another carriage return
bra ReadANewLine ;if not, get the next line and go again
;
;------------------------------------------------------------------------------
; This section of the main program loads each label from the Undefined Labels
; table (a table which holds all labels encountered in the Opcode field)
; against every label in the Valid Labels table until it either finds a match
; or finds that there is no duplicate label in the Valid Labels table. If the
; "Undefined" label turns out to have a counterpart on the Valid labels table,
; then no action is taken. If, however, the "undefined" label is truly
; undefined, then the label's name (resident in TempLabel because that's where
; it is put when it is checked against the valid list) is passed to the
; UndefError subroutine that prints an error message that includes the
; offending label's name.
;
;
EndProg movea.l #UndefLabels,A6 ;set ptr at begining of list
Loop cmpi.b #CR,(A6) ;End of list?
beq SecondPass ;if so, start assembly
movea.l #TempLabel,A5 ;if not set ptr to begining of templabel
1$ move.b (A6)+,(A5)+ ;copy a character from list to templabel
cmpi.b #null,(A6) ;end of this table entry?
bne 1$ ;if not keep copying until done w/it
clr.b (A5) ;if at end, place a null at end of temp
jsr DupCheck ;check if this undef appears on valid list
cmpi.b #0,DupFlag ;is it truly undefined?
beq UndefError ;If so tell the user
MoveAhead addq #1,A6 ;Move ahead to next entry
bra Loop ;check next entry
;
;------------------------------------------------------------------------------
; The following segment of code performs the final assembly of the half
; assembled code into native sim35 code.
;
;
SecondPass cmpi.b #1,ErrorFlag ;Error in first pass?
beq ToughLuck ;If so end assembler/simulator
jsr ClearScreen ;Clear the screen
movea.l #SecondMess,A0 ;If not, tell user second pass is on
jsr WriteString ;write this message
jsr WriteEOL ;produce a carriage return
movea.l #Program,A1 ;set ptr to begining of source
movea.l #$3000,A2 ;set ptr to begining of obj code
NextInstruction clr.w D0 ;clear space for first instruction
move.b (A1)+,D0 ;get an opcode
cmpi.b #$12,D0 ;end of assembly?
beq Simulate ;if so, then execute SIM35 program
clr.w D5 ;clear register for object code
cmpi.b #5,D0 ;is opcode <=5? (an RR)
bgt 1$ ;if not, check 2c if it is an RM
muls #16,D0 ;move opcode to second nibble
add.b D0,D5 ;put opcode in objective
clr.w D0 ;clear space for 1st operand
move.b (A1)+,D0 ;get first operand (hex num 0-3)
muls #4,D0 ;move 1st oprnd to bytes 3 and 2
add.b D0,D5 ;put first operand in objective
clr.w D0 ;clear space for second operand
move.b (A1)+,D0 ;get second operand (hex num 0-3)
add.b D0,D5 ;put second operand into objective
move.b D5,(A2)+ ;store objective in program
bra NextInstruction ;assemble next instruction
1$ cmpi.b #$C,D0 ;is opcode <=$C? (an RM)
bgt NoOpernds ;if not check 2c ifr it has no opernds
muls #$1000,D0 ;move opcode to 1st 4 bytes of word
add.w D0,D5 ;put opcode into objective
clr.w D0 ;clear space for 1st operand
move.b (A1)+,D0 ;get first operand
muls #$400,D0 ;place first operand after opcode
add.w D0,D5 ;put 1st operand in objective
cmpi.b #'9',(A1) ;is first character >9?
bgt LabelAddr ;if not it is a label address
movea.l A1,A0 ;pass parametyer for ASCII to decimal
jsr ASCII2Dec ;convert ASCII to decimal
add.w D0,D5 ;place second operand in objective
move.b D5,D6 ;store 1st half of objective temporarily
lsr.w #8,D5 ;get second half of objective
move.b D5,(A2)+ ;store 2nd half of objective in program
move.b D6,(A2)+ ;store 1st half of objective in program
bra NextInstruction ;Assemble next instruction
LabelAddr movea.l #TempLabel,A0 ;ptr for parameter passing
CopyChar move.b (A1)+,(A0)+ ;copy from source to TempLabel
cmpi.b #null,(A1) ;at end of Label?
bne CopyChar ;if not copy next character
move.b #null,(A0) ;put terminal char on templabel
jsr DupCheck ;find match on label list
add.w D6,D5 ;d6 holds address:put on objective
move.b D5,D6 ;store 1st half of objective temporarily
lsr.w #8,D5 ;get second half of objective
move.b D5,(A2)+ ;store 2nd half of objective in program
move.b D6,(A2)+ ;store 1st half of objective in program
addq.w #1,A1 ;account for null @ end of label
bra NextInstruction ;Assemble next instruction
NoOpernds cmpi.b #$F,D0 ;is opcode >$F?
bgt DataDirective ;if so it must be a DC or DS
muls #16,D0 ;if not, move opcode to mst sig nibble
add.b D0,D5 ;put opcode into objective
move.b D5,(A2)+ ;move objective code into program
bra NextInstruction ;assemble next instruction
DataDirective cmpi.b #$10,D0 ;is this a DC?
bne ItsaDS ;If not it is a DS
move.b (A1)+,(A2)+ ;if it is a DC, put const into program
bra NextInstruction ;Assemble next instruction
ItsaDS clr.w D0 ;clear space for # of bytes to skip
move.b (A1)+,D0 ;get high order of word
lsl.w #8,D0 ;move to high order position of word
move.b (A1)+,D1 ;get low order of word
add.w D1,D0 ;combine low and high order words
add.w D0,A2 ;leave those bytes blank
bra NextInstruction ;assemble next instruction
;
;------------------------------------------------------------------------------
; If an error occured in the first pass, then assembly cannot take place. The
; second pass is skiped and the simulation is skipped. The program jumps
; straight to the end. I call it tough luck because my assembler is soooo user
; unfriendly that if you make one little error you must reenter the whole
; program again (you can't even use the backspace key). Tough Luck indeed!
;
;
ToughLuck movea.l #CantAssem,A0 ;ptr to tough luck message
jsr WriteString ;display error
jsr WriteEOL ;produce a carraige return
bra Finito ;end the assembler/simuilator
;
;------------------------------------------------------------------------------
; The Simiulate portion of this program reads native SIM35 code from memory
; starting at $3000, and extending to $33FF. These addresses are used to
; simulate the 10 bits of addressing space of the SIM35. The DPR and DPM
; instructions have not been implemented, they are treated as a NOP. A byte in
; main memory (within the data block) has been set aside for the simulated
; condition code. Often, the simulator will copy the m68000 condition code
; into this memory location in order to keep the integrity of the sim35
; condition code while the 68000 process other instructions.
;
;
Simulate movea.l #ProgRun,A0 ;set ptrto show message
jsr WriteString ;Display message
jsr WriteEOL ;produce a carriage return
movea.l #$3000,A0 ;set ptr to begining of simulated memory
DoInst clr.l D4 ;clear the opcode register
clr.l D5 ;clear a working register
move.b (A0)+,D4 ;get an instruction
move.b #16,D5 ;binary 10000
divs D5,D4 ;opcode in LOword,operands in HOword
swap D4 ;revers order in above comment
clr.l D5 ;clear register for source operand
clr.l D6 ;clear register for dest operand
move.b D4,D5 ;put source and dest in dest register
swap D4 ;Opcode in Low Order word
move.b #4,D6 ;binary 100
divs D6,D5 ;dest reg in LOword,source in HOword
move.b D5,D6 ;dest reg in D6
swap D5 ;source reg in D5
cmpi.b #5,D4 ;is opcode >5?
bgt MemInst ;If so it may have an address operand
cmpi.b #0,D5 ;Is source reg=0?
bne 1$ ;if not, it may be 1
move.b D0,D5 ;if it is 0, put value in D5
bra Arithmetic ;execute instruction
1$ cmpi.b #1,D5 ;Is source reg=1?
bne 2$ ;if not, it may be 2
move.b D1,D5 ;if it is 1, put value in D5
bra Arithmetic ;execute instruction
2$ cmpi.b #2,D5 ;Is source reg=2?
bne 3$ ;if not, it must be 3
move.b D2,D5 ;if it is 2, put value in D5
bra Arithmetic ;execute instruction
3$ move.b D3,D5 ;put value in D5
bra Arithmetic
MemInst cmpi.b #$D,D4 ;Is this a no operand instruction?
bge ExitOrNot ;if so, check 2c if it is an EXT
clr.l D7 ;clear space for memory address
move.b (A0)+,D7 ;get next byte (last 8 bits of address)
muls #256,D5 ;move 1st two bits to bits 9 and 8
add.w D5,D7 ;put bits 9 and 8 with 7-0
add.w #$3000,D7 ;convert to simulated address
movea.l D7,A1 ;prepare to get value from memory
cmpi.b #$C,D4 ;is this a store memory?
beq MemoryStg ;If so, deal with it elsewhere
cmpi.b #6,D4 ;is it a branch instruction?
beq BranchIns ;If so, deal with it elsewhere
move.b (A1),D5 ;store value from memory in source
subi.b #7,D4 ;make opcode equivalent to RR version
cmpi.b #2,D4 ;is it a multiply or divide?
bgt 1$ ;if so, move opcode foreward 1 (skip NLR)
bra Arithmetic ;if not, execute the instruction
1$ addq.b #1,D4 ;move opcode foreward 1
bra Arithmetic ;execute instruction
ExitOrNot cmpi.b #$D,D4 ;is it an EXT instruction?
bne DoInst ;If not, process next instruciton
bra Finito ;If so, end program
Arithmetic move.b D6,DestReg ;make a copy of the destination register
cmpi.b #0,D6 ;is the destination register =0?
bne 1$ ;if not keep checking
move.b D0,D6 ;if so store value in D6
bra DoMath ;Add,sub,Div,Mult,etc
1$ cmpi.b #1,D6 ;is the destination register =1?
bne 2$ ;if not keep checking
move.b D1,D6 ;if so store value in D6
bra DoMath ;Add,sub,Div,Mult,etc
2$ cmpi.b #2,D6 ;is the destination register =2?
bne 3$ ;if not it must be 3
move.b D2,D6 ;if so store value in D6
bra DoMath ;Add,sub,Div,Mult,etc
3$ move.b D3,D6 ;store value in D6
DoMath ext.w D5 ;sign extend the source
ext.l D5 ;sign extend the source
ext.w D6 ;sign extend the destination
ext.l D6 ;sign extend the destination
cmpi.b #0,D4 ;is it an add?
bne 1$ ;if not check 2c if it is a sub
add.b D5,D6 ;add source to destination
bra UpdateCC ;Update the simulated CC
1$ cmpi.b #1,D4 ;is it a subtract?
bne 2$ ;if not, check 2c if it is a LR
sub.b D5,D6 ;subtract source from destination
bra UpdateCC ;Update the simulated CC
2$ cmpi.b #2,D4 ;is it a LR?
bne 3$ ;if not, check 2c if it is a NLR
move.b D5,D6 ;move source into destination
bra UpdateCC ;Update the simulated CC
3$ cmpi.b #3,D4 ;is it a NLR?
bne 4$ ;if not, check 2c if it is a multiply
neg.b D5 ;negate source
move.b D5,D6 ;move source into destination
bra UpdateCC ;Update the simulated CC
4$ cmpi.b #4,D4 ;is it a multiply?
bne 5$ ;if not it must be a divide
muls D5,D6 ;multiply destination by source
bra UpdateCC ;Update the simulated CC
5$ divs D5,D6 ;divide the destination by the source
UpdateCC move.w sr,(CondCode) ;move condition code into simulated CC
StoreResult move.b (DestReg),D5 ;get orriginal destination register
cmpi.b #0,D5 ;Is dest reg=0?
bne 1$ ;if not, it may be 1
move.b D6,D0 ;if it is 0, put value in D0 (R0)
bra DoInst ;Process next instruction
1$ cmpi.b #1,D5 ;Is dest reg=1?
bne 2$ ;if not, it may be 2
move.b D6,D1 ;if it is 1, put value in D1 (R1)
bra DoInst ;Process next instruction
2$ cmpi.b #2,D5 ;Is dest reg=2?
bne 3$ ;if not, it must be 3
move.b D6,D2 ;if it is 2, put value in D2 (R2)
bra DoInst ;Process next instruction
3$ move.b D6,D3 ;put value in D3 (R3)
bra DoInst ;Process next instruction
MemoryStg cmpi.b #0,D6 ;is the source register =0?
bne 1$ ;if not keep checking
move.b D0,D6 ;if so store value in D6
bra StoreIt ;Store the value
1$ cmpi.b #1,D6 ;is the source register =1?
bne 2$ ;if not keep checking
move.b D1,D6 ;if so store value in D6
bra StoreIt ;Store the value in memory
2$ cmpi.b #2,D6 ;is the source register =2?
bne 3$ ;if not it must be 3
move.b D2,D6 ;if so store value in D6
bra StoreIt ;Store the value in memory
3$ move.b D3,D6 ;store the value in memory
StoreIt move.b D6,(A1) ;store value in memory
move sr,CondCode ;store CC in simulated CC
bra DoInst ;Process next instruction
BranchIns cmpi.b #0,D6 ;Is it a BRA?
bne BEQ ;if not it may be a BEQ
bra TakeBranch ;if so, then take the branch
BEQ cmpi.b #1,D6 ;is it a BEQ?
bne BGT ;if not it may be a BGT
btst #2,(CondCode+1) ;test zero bit
bne TakeBranch ;if it is set, then take the branch
bra DoInst ;otherwise, process next instruction
BGT cmpi.b #2,D6 ;is it a BGT?
bne BLT ;if not it must be a BLT
btst #2,(CondCode+1) ;test the zero bit
bne DoInst ;if it is set, don't branch
btst #3,(CondCode+1) ;test the N bit
beq TakeBranch ;If both N&V are reset take the branch
bra DoInst ;if they differ, process next instruction
BLT btst #3,(CondCode+1) ;test the N bit
bne TakeBranch ;if both V&N nare set, take the branch
bra DoInst ;if they are same, don't branch
TakeBranch movea.l A1,A0 ;set simulated PC to reflect branch
bra DoInst ;implement instruction at new location
;
;------------------------------------------------------------------------------
; This is a standard exit
;
;
Finito move #228,D7
trap #14
*****************************
* *
* SUBROUTINES *
* *
*****************************
;
;------------------------------------------------------------------------------
; The Scan subroutine moves through the Input line and copies it into the
; stretch of memory that is pointed to by A5 (the temporary pointer). It
; continues to copy characters until it hits a space (end of field, so time to
; change where temporary pointer points to) or a carriage reutrn (end of input
; so stop scanning altogether by BRANCHING back to continuation point). Since
; this subroutine eventually branches back (rather than returns) a pop of the
; stack is the first action taken when the branch is taken (to the Analyze
; block).
;
;
Scan move.w #39,D0 ;Maximum no. of characters per field
1$ cmpi.b #null,(A4) ;Is the Input ptr at the end?
beq Analyze ;If so BRANCH back (popped later)
cmpi.b #space,(A4) ;If not, check if ptr is at end of field
beq Return ;If it is, Scan routin complete
move.b (A4)+,(A5)+ ;If not, copy a character into temporary
move.b #null,(A5) ;Put end of field marker (eof) behind it
dbra D0,1$ ;branch to move next (unless > 40 chars)
Return rts ;normal return from subroutine
;
;------------------------------------------------------------------------------
; The SkipSpaces routine simply skips over intervening spaces between fields.
; If it encounters an end of line it cannot differentiate between it and
; another character, and since the ptr is left pointing to the first available
; character, the Scan routine will pick up this case.
;
;
SkipSpaces cmpi.b #space,(A4)+ ;check to see if we're at a space & incr
beq SkipSpaces ;if so move ahead
subq #1,A4
rts ;if not, our ptr points to next character
;
;------------------------------------------------------------------------------
; The ExamineLabel routine calls LabelCheck and Dupcheck to determine if a
; label is first valid and second duplicated. If the label fails either test
; (boolean flags are returned from the two subroutines to indicate the success
; or failure of a particular label) then the appropriate error message is given.
; In particular, when the label is found to be invalid, a short routine that
; is called InvalidLabel handels the issuance of Invalid Label errors. If
; the label passes these tests, however, ExamineLabel jumps to a branch of
; itself called ItsOK. ItsOK puts the new, valid label into the ValidLabels
; list. The first part of ItsOK traverses this list to the first empty spot.
; The next section (labeled PutInList) actually places the label name along
; with the address that the label corresponds to into the
; next available slot in the list. The last section, called FullNulls pads the
; Label name with nulls so that it takes up 12 bytes exactly. This code
; segment also replaces the end of list marker (cariage return) after this
; newest addition to the list.
;
;
ExamineLabel movea.l #Label,A4 ;points to beginning of Label field
cmpi.b #null,(A4) ;Is there a label?
beq ExitRoutine ;If not, exit this routine
cmpi.b #'$',(A4)+ ;is first char a "$"?
bne InvalidLabel ;if not, label is invalid
movea.l #TempLabel,A5 ;set ptr to begining of temp label
1$ cmpi.b #0,(A4) ;at end of label field?
beq 2$ ;if so, finish templabel and continue
move.b (A4)+,(A5)+ ;move character in TempLabel
bra 1$ ;see if whole label copied, again if not
2$ move.b #0,(A5) ;put terminal null into TempLabel
jsr LabelCheck ;checks to see if it is valid
cmpi.b #0,ValidFlag ;is flag set to valid (true=0)
bne InvalidLabel ;if not, label is invalid
jsr DupCheck ;checks to see if label is a duplicate
cmpi.b #0,DupFlag ;is flag set to non-duplicate (0=false)
beq ItsOK ;if so, label is ok to add to table
movea.l #DuplicateLab,A0 ;if not, move ptr to begining of err msg
jsr WriteString ;write error message
jsr WriteEOL ;produce a carriage return
rts ;return to Analayze for Opcode analasys
ItsOK movea.l #ValidLabels,A4 ;move ptr to begining of list
1$ cmpi.b #$FF,(A4)+ ;at end of list yet?
bne 1$ ;if not keep moving until at E.O.L.
subq #1,A4 ;if we are move ptr onto E.O.L. marker
movea.l #TempLabel,A5 ;set ptr to begining of label to add
move.w (Object.Ptr),(A4)+ ;1st 2 bytes of entry show address
move #9,D0 ;counter for 10 characters to be read
PutInList move.b (A5)+,(A4)+ ;copy a character from templabel to list
subq #1,D0 ;take away one for each character in lbl
cmpi.b #null,(A5) ;at end of label?
bne PutInList ;if not keep copying characters
FillNulls move.b #null,(A4)+ ;put a null at end of label
dbra D0,FillNulls ;add nulls 'till 10 chars entered tot.
move.b #$FF,(A4) ;put E.O.L. marker in list
ExitRoutine rts ;go back to Analyze (to look at Opcodes)
;
;------------------------------------------------------------------------------
; The invalid label routine displays the invalid label error message and
; returns control to the main program (the Analyze block).
;
;
InvalidLabel movea.l #InvalidLab,A0 ;tell user that his label...
jsr WriteString ; ...is invalid
jsr WriteEOL ;produce a carriage return
move.b #1,ErrorFlag ;set flag to show that error ocurred
rts ;Go back to Analyze
;
;------------------------------------------------------------------------------
; The LabelCheck routine recives a string whose first character is stored in
; TempLabel and who is expected to be a valid label. If this is called from
; examen label, the calling routine already checked to see that a dollar sign
; ($) preceded this string. If the calling routine was ExamineOpcodes, such a
; check was not necessary. In all cases, valid labels start with a letter, so
; this routine first makes sure that the first character is a letter (upper
; case). Beyond that, this routine makes sure that there are no more than nine
; characters, that the label is terminated by a colon (:) followed by a #null,
; and that the the intermittent characters are alphanumeric. If the label
; passes all of these tests, then its flag is left with a value of 0 (=valid
; label). If not, the flag is set to 1 (invalid label). The calling
; subroutine uses the status of the flag to decide what course of action to
; take.
;
;
LabelCheck move.b #0,ValidFlag ;set boolean flag to say label is valid
movea.l #TempLabel,A5 ;set pointer to temporary string holder
cmpi.b #'A',(A5) ;check to see if character < 'A'
blt Invalid ;if so it is invalid
cmpi.b #'Z',(A5)+ ;check to see if character > 'Z'
bgt Invalid ;if so it is invalid
Check move #5,D0 ;# of iterations (1st char+ 6 chars + ":")
Again cmpi.b #null,(A5) ;Is character a null?
beq Invalid ;If so, then lable is invalid
cmpi.b #':',(A5) ;at end of label?
beq EndOfLabel ;if so make a final check
cmpi.b #'Z',(A5) ;>'Z'?
bgt Invalid ;if so it is invalid
cmpi.b #'0',(A5) ;<'0'?
blt Invalid ;if so it is invalid
cmpi.b #'9',(A5) ;compare to "9"
ble NextChar ;if <="9" then it is ok, check next
cmpi.b #'A',(A5) ;compare to "A"
bge NextChar ;if >="A" then it is a letter, OK so far
bra Invalid ;if no checks passed, it is invalid
NextChar addq #1,A5 ;increment ptr to next character
dbra D0,Again ;decrement count and read next character
cmpi.b #':',(A5) ;is 9th character a colon?
bne Invalid ;if not it is invalid
EndOfLabel addq #1,A5 ;look at next character
cmpi.b #0,(A5) ;is this the last character?
bne Invalid ;if not, then the label is invalid
rts ;alls well, return to ExamenLabel
Invalid move.b #1,ValidFlag ;set ValidFlag to false (invalid=1)
rts ;return to ExamenLabel
;
;------------------------------------------------------------------------------
; The DupCheck routine compares the string with starting address tempstring
; to all the strings recorded in the ValidLabels Table. If it finds a match
; it sets the flag (DupFlag) to 1, otherwise it sets it to 0. The usefulness
; of this information is dependant upon the calling subroutine. If LabelCheck
; calls it, a duplicate result (DupFlag=1) causes an error (duplicate label
; error) to occur. If ExamineOpcodes was the calling routine, then a no
; duplicate result (DupFlag=0) would produce an error (undefined label error)
; In the second pass, DupCheck is used to match opcodes to their
; location numbers so the first 2 bytes of each label are stored in
; a data register (D6) as each label is checked.
;
;
DupCheck move.b #0,DupFlag ;Not a duplicate yet
movea.l #TempLabel,A5 ;set ptr to begining of label to check
movea.l #ValidLabels,A4 ;set ptr to begining of Valid Label list
cmpi.b #$FF,(A4) ;is list empty?
beq Done ;cannot be a duplicate if list is empty
CheckALabel move.w (A4)+,D6 ;save address for use by 2nd pass
move.w #9,D0 ;counter to see how far to skip to next
CheckChar subq.b #1,D0 ;one less character to skip to next lbl
cmpm.b (A4)+,(A5)+ ;are they duplicate characters?
bne NextLabel ;If they aren't equal, check against next
cmpi.b #null,(A4) ;Is this the end of the label?
beq ItsADup ;If so, then we have a duplication
bra CheckChar ;If not, check next character
NextLabel addq.w #1,A4 ;move forward 1 character
dbra D0,NextLabel ;move ahead till this entry is passed
cmpi.b #$FF,(A4) ;is this the end of the list?
bne LookAgain ;if not set ptr in TempLabel to begining
Done rts ;if so, label is not a duplication
LookAgain movea.l #TempLabel,A5 ;set ptr in TempLabel to begining
bra CheckALabel ;start checking the next label
ItsADup move.b #1,DupFlag ;set flag to show it is a duplicate
rts ;return to calling subroutine
;
;------------------------------------------------------------------------------
; The ExamineOpcode subroutine first checks to see if the Opcode field is
; empty. If it is then it displays a missing opcode error and returns to the
; Analyze block. Otherwise, it checks the characters in the Opcode Files
; versus the characters of the first Opcode in the table. If this does not
; form a match all the way up to null in the opcode field and "1" in the table
; ("1" is the separatetor between the menomnic and the opcode in the table),
; then it resets the pointer to the begining of the Opcode field and moves the
; table pointer ahead until it is at the begining of the next mnemonic. If
; this goes on all the way through the entire table without an exact match,
; then the user is furnished with an invalid opcode error. If however the
; mnemonic turns out to be valid, then two things happen. First, the ptr in the
; object code is incremented the appropriate ammount (1 or 2 bytes except in the
; case of DS and DC). Second, the propoer opcode (a word length hex integer) is
; placed into memory (starting at Program for the first command). In either
; case (valid or invalid) a value must be chosen for the OperandType [0=RR,
; 1=RM, 2=none]. Since the operand arrived at by this subroutine is in ASCII
; form, inequalities that test which group a particualr opcode falls into must
; use the ASCII values of the opcodes. Between the ASCII value for 0 and the
; ASCII value for 5 the OperandType is RR (0). Above 5 but below D (it does
; not matter that there are intervening characters between the numbers and the
; letters in ASCII, the operand can never be one of these intervening characters
; so we can act as if they were not there) the OperandType is RM (1). At D and
; above there are no operands (type2). This information is stored in
; OperandType (location in memory) for the next major subroutine
; (ExamineOperands) to access. Opcodes $10 and $11 (DC and DS) also use
; OperandType 2 which causes the ExamineOperands routine to ignore their
; operands. The operand of these instructions is handled in a special
; subroutine.
;
;
ExamineOpcode movea.l #Opcode,A4 ;ptr to begining of Opcode field
cmpi.b #0,(A4) ;Is this field empty?
beq MisNOp ;If so we are mising an Operand
movea.l #OpTable,A5 ;ptr to opcode table
CheckOp movea.l #Opcode,A4 ;ptr to begining of Opcode field
CheckOpChar cmpm.b (A4)+,(A5)+ ;do we have a match?
bne NextOpcode ;if not, see what is the next on table
cmpi.b #$FE,(A5) ;at the dividing character?
bne CheckOpChar ;if not check the next character
cmpi.b #0,(A4) ;if so are we out of characters in temp?
bne NextOpcode ;if not, see what is next on the table
addq #1,A5 ;if we have a match, then skip to opcode
move.b (A5),OpcodeVal ;Put opcode for mnemonic in OpcodeVal
bra ValidOp ;it is valid:add to object.ptr and source
NextOpcode cmpi.b #$FF,(A5)+ ;if not, then see if we're at next opcode
bne NextOpcode ;if not move until we are there
cmpi.b #CR,(A5) ;at end of table?
beq InvalidOp ;if so, mnemonic in temp is invlaid
bra CheckOp ;if not we're at next opcode, check it.
ValidOp cmpi.b #$12,OpcodeVal ;Did we just have an END directive?
beq EndDirective ;If so then deal with it accordingly
cmpi.b #$5,OpcodeVal ;Is opcode>5
bgt Type1or2 ;If so, set Operand value accordingly
move.b #0,OperandType ;If not it is RR type,
bra OpcodeStuff ;Increment ptr and do 1/2 assembly
Type1or2 cmpi.b #$C,OpcodeVal ;Is opcode >$C?
bgt Type2 ;if so, set Operand value accordingly
move.b #1,OperandType ;if not it is type 1
bra OpcodeStuff ;Increment ptr and do 1/2 assembly
Type2 move.b #2,OperandType ;it must be opearand type 2
OpcodeStuff cmpi.b #$10,OpcodeVal ;Is opcode a DC or DS?
bge DfnDirective ;If so, deal with it in a subroutine
movea.l (Prog.Ptr),A0 ;1/2 ptr=location of next intruction
move.b (OpcodeVal),(A0)+ ;Store opcode in 1/2 assm format
move.l A0,Prog.Ptr ;Increment 1/2 assm ptr
cmpi.b #1,OperandType ;Is this Operand Type RM?
bne RR ;If not, 1 byte displacement is needed
addq.w #1,(Object.Ptr) ;If so add an extra byte displacement
RR addq.w #1,(Object.Ptr) ;move ahead 1 byte in object code
rts ;return to analyze
MisNOp movea.l #MissingOpcode,A0 ;set ptr to error message
jsr WriteString ;display error message
jsr WriteEOL ;produce a carriage return
move.b #1,ErrorFlag ;Set flag to show that an error occured
rts ;Return to Analyze
InvalidOp movea.l #InvalidOpcode,A0 ;ptr to error string
jsr WriteString ;show user his error
jsr WriteEOL ;produce a carriage return
move.b #0,OperandType ;assumption:invalid opcodes are RR
move.b #1,ErrorFlag ;Set flag to show that an error occured
rts ;return to analyze
EndDirective movea.l (Prog.Ptr),A0 ;set ptr to next available space in source
move.b #$12,(A0) ;put end directive in source (1/2 assm)
move.b #1,EndofProg ;set program ending flag
rts ;return to analyze
DfnDirective move.b #0,NegFlag ;set sign of operand to positive (for now)
movea.l #Operands,A0 ;move ptr to begining of operand field
cmpi.b #'-',(A0) ;is this a negative number?
bne 1$ ;if not, do not set negation flag
move.b #1,NegFlag ;number is negative
addq.l #1,A0 ;point to first digit, past '-' character
1$ jsr ASCII2Dec ;convert to ASCII into a hex number
cmpi.b #1,ValidFlag ;Check 2c if operand was invalid
beq Inv ;if so, deliver error message
cmpi.b #1,NegFlag ;is this a negative number?
bne ProcessDir ;if not go ahead &see if it is DS or DC
neg.w D0 ;if it is negative, negate value first
ProcessDir movea.l (Prog.Ptr),A0 ;set ptr to source (1/2 assembled)
move.b (OpcodeVal),(A0)+ ;store opcode in source
cmpi.b #$10,OpcodeVal ;is this a DC?
bne Storage ;if not it is a DS
move.b D0,(A0)+ ;store operand in source
move.l A0,Prog.Ptr ;store incremented pointer
addq.w #1,Object.Ptr ;make space for a 1 byte constant
rts ;return to Analyze
Storage move.w D0,D1 ;copy the operand
lsr #8,D1 ;get first byte of operand
move.b D1,(A0)+ ;store first byte of operand in source
move.b D0,(A0)+ ;store second byte of operand in source
move.l A0,Prog.Ptr ;store incremented pointer
tst.w D0 ;Is the opcode negative?
blt Inv ;If so it is invalid
add.w D0,Object.Ptr ;if not, move ahead # of bytes=to operand
rts ;return to Analyze
Inv movea.l #Inval1Oprnd,A0 ;ptr to error message
jsr WriteString ;display error message
jsr WriteEOL ;produce a carriage return
move.b #1,ErrorFlag ;set flag to show that na error occured
rts ;return to Analyze
;
;------------------------------------------------------------------------------
; The ExamineOperand Subroutine checks both the first and second operands of an
; instruction. Since there are three possibilities for the correct configuration
; of operands (depending upon which opcode was entered), this routine first
; checks to see if we need no operands at all (type 2) If we do not need them,
; then we go back to the main program (Analyze) without checking any further.
; If it is either type RR or RM (0 and 1 respectively), then we check to make
; sure the operand field is not empty. If it is missing operand errors are
; displayed. Once we know there is something in the field, we check the first
; operand. If it is not and integer between 0 and 3 inclusive and error will
; be printed (either invalid operand error or missing operand error).
; Regardless of the validity of the first operand, the second operand's validity
; is tested. If the type is RR, then the second operand must be and integer
; between 0 and 3 (the test for this is identical to the test used for the first
; operand, but the code is repeated-like a macro would produce). If the second
; operand is not 0-3, then either an invalid second operand error will occur,
; or a missing operand error will occur, whichever is appropriate. If the type
; is RM, then the operand can be either a number from 0 to 1023 or a valid
; label (sans the $). If this type of label is expected, the first character is
; tested. If it is >=0 and <=9 it is assumed that it is going to be an integer.
; The length of the integer is tested. If it only has three characters, then it
; is valid as long as the other two characters are digits. If it has four
; characters, then the fist must be a 1 for validity. The second must be a 0.
; These comparisons are dirrect, if either one fails, the address is thrown out
; as invalid. The thrid character must be either a 0, 1, or 2. If it is a 0 or
; 1, then the last character is checked to see if it is a digit, if so, the
; address is valid. If the third character is a 2, then the last character
; must be a digit between 0 and 3 inclusive. If this is so, then the operand is
; valid. If not an invalid operand error is displayed. If, however, the first
; character of the second operand is not a digit, then it is checked to see if
; it is a label (in MayBeLabel branch). The previously defined LabelCheck
; routine determines the validity of the label, and the boolean flag it returns
; is used determine this routine's course of action. If the label is not valid
; (ValidFlag = 1), then an invalid label error is produced. If the label is
; valid, then it is added to the end of the Undefined Labels list. This list
; does not actually represent Undefined Labels, but it instead represents all
; the labels that could be undefined. This is the set of all labels encountered
; as an operand. At the end of the program, these "Undefined Labels" are
; checked against the valid label list to see if there are any that really are
; undefined. UndefError handles this process and is described in the following
; section. If the operands are valid, then the number 0-3 is stored in the
; source (1/2 assembled code) and memory locations and labels are stored as
; strings.
;
;
ExamineOperand cmpi.b #2,OperandType ;Is this an opcode w/o operands?
bne CheckOperands ;If not we have to check the operands
rts ;if it is we go no problems, return
CheckOperands movea.l #Operands,A4 ;move ptr to begining of operands field
cmpi.b #null,(A4) ;is field empty?
bne CheckFirst ;I hope not, we need two operands
movea.l #Miss1Operand,A0 ;If so, get set for first error.
jsr WriteString ;Print first error
jsr WriteEOL ;produce a carriage return
move.b #1,ErrorFlag ;Set flag to show that an error occured
MissSecond movea.l #Miss2Operand,A0 ;Get set for missing second operand err
jsr WriteString ;Print second error
jsr WriteEOL ;produce a carriage return
move.b #1,ErrorFlag ;Set flag to show that an error occured
rts ;that's it, we've got error(s) in ops
CheckFirst cmpi.b #',',(A4) ;if first operand missing?
bne 2$ ;if not then proceed
movea.l #Miss1Operand,A0 ;but if it is, relinquish error mssg.
jsr WriteString ;print error message
jsr WriteEOL ;produce a carriage return
move.b #1,ErrorFlag ;Set flag to show that an error occured
bra CheckSecond ;look at second operand
2$ cmpi.b #'0',(A4) ;is first char <'0'?'
blt 3$ ;If so first operand is illegal
cmpi.b #'3',(A4)+ ;is first character >'3'?
bgt 3$ ;If so first operand is illegal
cmpi.b #null,(A4) ;is that all?
beq MissSecond ;if so, second is missing
cmpi.b #',',(A4) ;are we at the 2nd operand yet?
beq StoreFirst ;if so check it for validity
3$ movea.l #Inval1Oprnd,A0 ;if not at end of first yet,1st invald
jsr WriteString ;print error message
jsr WriteEOL ;produce a carriage return
move.b #1,ErrorFlag ;Set flag to show that an error occured
4$ cmpi.b #',',(A4) ;at comma yet?
beq StoreFirst ;if so, 1st is OK-check second
cmpi.b #0,(A4)+ ;Is that all (nhothing after comma)
beq MissSecond ;If so we are missing second operand
bra 4$ ;otherwise, keep looking for comma
StoreFirst subq.l #1,A4 ;point to byte showing 1st oprnd reg
move.b (A4)+,D0 ;copy ASCII into a temporary register
subi.b #$30,D0 ;convert from ASCII to decimal
movea.l (Prog.Ptr),A0 ;get address of ptr in 1/2 assmbly
move.b D0,(A0)+ ;copy hex operand in source (1/2 asm)
move.l A0,Prog.Ptr ;increment pointer to next byte
CheckSecond addq #1,A4 ;move to 1st char of 2nd op
movea.l #TempLabel,A5 ;set ptr in TempLabel
cmpi.b #0,(A4) ;is there a second operand?
bne 1$ ;if there is go ahead and examine it
bra MissSecond ;If not, then display error
1$ move.b (A4)+,(A5)+ ;Copy a character into TempLabel
cmpi.b #0,(A4) ;is that all?
bne 1$ ;if not, continue to copy
move.b (A4),(A5) ;if so put a null at end of TempLabel
movea.l #TempLabel,A5 ;reset pointer
cmpi.b #1,OperandType ;Is second opperand a memory address?
beq MemAddr ;If so then deal with it as such
cmpi.b #'0',(A5) ;if not, it first character a '0'?
blt Invalid2nd ;if it is <'0', then it is invalid
cmpi.b #'3',(A5)+ ;is 1st char >'3'?
bgt Invalid2nd ;if so, it is invalid
cmpi.b #0,(A5) ;Are there any other characters?
bne Invalid2nd ;If there are, then 2nd operand invalid
subq.l #1,A5 ;point to byte showing 1st oprnd reg
move.b (A5)+,D0 ;copy ASCII into a temporary register
subi.b #$30,D0 ;convert from ASCII to decimal
movea.l (Prog.Ptr),A0 ;get address of ptr in 1/2 assmbly
move.b D0,(A0)+ ;copy hex operand in source (1/2 asm)
move.l A0,Prog.Ptr ;increment pointer to next byte
rts ;otherwise, 2nd is OK-return to Analyze
Invalid2nd movea.l #Inval2Oprnd,A0 ;set ptr to error message
jsr WriteString ;Display error message
jsr WriteEOL ;produce a carriage return
move.b #1,ErrorFlag ;Set flag to show that an error occured
rts ;return to Analyze
MemAddr cmpi.b #'0',(A5) ;Is first char <'0'?
blt MaybeLabel ;It doesn't start w/a# it maybealable
cmpi.b #'9',(A5) ;Is first char >'9'?
bgt MaybeLabel ;Dosen't start w/a#, May be a Label
move #4,D0 ;Character counter
1$ cmpi.b #0,(A5)+ ;at end of label?
dbeq D0,1$ ;if not,check next(but exit if>4chars)
move #4,d1 ;this value used to calculate # of chars
sub D0,D1 ;now D1 holds actual number of chars
movea.l #TempLabel,A5 ;Set ptr to begining
cmpi.b #3,D1 ;is # of chars<=3?
bgt FourChars ;Then It must have four chars
ThreeOrLess addq.l #1,A5 ;Skip first char "x", we know 0 <= x <= 9
TestADigit cmpi.b #null,(A5) ;at the end?
beq ExitOK ;if so, operand is good
cmpi.b #'0',(A5) ;Is character <'0'?
blt Invalid2nd ;If so operand is invalid
cmpi.b #'9',(A5)+ ;is character >'9'?
bgt Invalid2nd ;If so operand is invalid
bra TestADigit ;if it was ok, test next digit
FourChars cmpi.b #4,D1 ;Are ther four characters?
bne Invalid2nd ;If not then it is invalid
cmpi.b #0,(A5) ;Is 1st char a zero?
beq ThreeOrLess ;If so check as a three character #
cmpi.b #'1',(A5)+ ;Is 1st char a '1'?
bne Invalid2nd ;If not it cannot be valid
cmpi.b #'0',(A5)+ ;Is 2nd char a '0'?
bne Invalid2nd ;If not, it cannot be valid
cmpi.b #'0',(A5) ;Is third char <'0'?
blt Invalid2nd ;If so label is invalid
cmpi.b #'2',(A5)+ ;Is third char a 1 or 0?
blt 1$ ;If so check fourth character
bne Invalid2nd ;If 3rd is not otherwise a 2 is invalid
cmpi.b #'0',(A5) ;If 4th <'0'?
blt Invalid2nd ;If so then invalid
cmpi.b #'3',(A5) ;Is 4th >'3'?
bgt Invalid2nd ;If so then invalid
bra ExitOK ;otherwise, its valid
1$ cmpi.b #'0',(A5) ;is 4th char<'0'?
blt Invalid2nd ;If so then invalid
cmpi.b #'9',(A5) ;is 4th char>'9'?
bgt Invalid2nd ;If so then it is invalid
bra ExitOK ;otherwise, its valid
MaybeLabel jsr LabelCheck ;use subroutine to check validity
cmpi.b #0,ValidFlag ;Is label valid?
bne Invalid2nd ;If not it is invalid
movea.l #TempLabel,A5 ;set ptr back to begining
movea.l #UndefLabels,A4 ;set ptr to begining of undefined table
1$ cmpi.b #CR,(A4)+ ;at end of undef label list?
bne 1$ ;loop until end is reached
subq #1,A4 ;move pointer last step to very end
2$ move.b (A5)+,(A4)+ ;copy a character
cmpi.b #0,(A5) ;End of label?
bne 2$ ;loop until end of label is reached
move.b (A5),(A4)+ ;place null on undefined label list
move.b #CR,(A4) ;place and end of list mark on undef list
ExitOK movea.l #TempLabel,A5 ;set ptr to begining of label
movea.l (Prog.Ptr),A0 ;set ptr to next space in source
1$ move.b (A5)+,(A0)+ ;copy a character into source
cmpi.b #null,(A5) ;at end of label?
bne 1$ ;if not keep copying till done
move.b #null,(A0)+ ;if so, put end of label mark in source
move.l A0,(Prog.Ptr) ;record updated ptr position
rts ;label is ok, return to Analyze
;
;------------------------------------------------------------------------------
; The ASCII2Dec routine converts an ASCII string of digits that represent a
; decimal number into their corresponding hex value. It recives a pointer to
; the string in A0, and places the final hex number in D0.
;
;
ASCII2Dec move.b #0,ValidFlag ;Operand is not invalid yet
clr.w D0 ;This will hold the number
clr.w D1 ;set digit counter to 0
DigitCount cmpi.b #0,(A0)+ ;at end of operand?
beq BackToBeg ;if so, move ptr to begining of operand
addq.w #1,D1 ;if not, then increment digit counter
bra DigitCount ;and look for next digit
BackToBeg addq.b #1,D1 ;adjust for last postincrements
add.w D1,A1 ;move ahead in obj code during 2nd pass
suba.w D1,A0 ;move ptr back to begining of operand
subq.b #1,D1 ;set digit count back to correct #
NextDigit cmpi.b #'0',(A0) ;is next digit <0?
blt Inval ;if so, it is invalid
cmpi.b #'9',(A0) ;is next digit >9?
bgt Inval ;If so, it is invalid
clr.w D2 ;clear space for hex digit
move.b (A0),D2 ;put ASCII into a register
subi.b #$30,D2 ;convert to a decimal digit
cmpi.w #1,D1 ;is this the last digit (digit ctr=1)?
beq LastDigit ;if so, add final digit & exit routine
move.w D1,D3 ;if not, prepare an exponent of 10
move.w #1,D4 ;initalize multiplier
subq.w #2,D3 ;account for first multiple
Multiple muls #10,D4 ;increase by a power of ten
dbra D3,Multiple ;reduce exponent by one until done
muls D4,D2 ;multiply digit by its place value
add.w D2,D0 ;add this number to total
addq.l #1,A0 ;move to next digit
subq.w #1,D1 ;reduce power
bra NextDigit ;process next digit
LastDigit add.w D2,D0 ;add final digit (times 1)
rts ;end routine
Inval move.b #1,ValidFlag ;Set flag to show that label is invalid
rts ;end routine
;
;------------------------------------------------------------------------------
; The UndefError routine moves the label's name (held in memory starting at
; TempLabel) to memory starting at UdLabelName. This memory location is
; dirrectly after the string which makes up the undefined error message. So
; this routine embeds the name of the undefined label into the error message,
; and then prints the message.
;
;
UndefError movea.l #TempLabel,A5 ;set ptr to begining of undefined label
movea.l #UdLabelName,A3 ;set ptr to "fill in the blank" in messg.
2$ move.b (A5)+,(A3)+ ;copy a character
cmpi.b #null,(A5) ;end of undefined label?
bne 2$ ;if not continue copying until done
clr.b (A3) ;set end of label mark in message
movea.l #UDLabelErr,A0 ;set pointer to label error
jsr WriteString ;write error message
jsr WriteEOL ;produce a carriage return
move.b #1,ErrorFlag ;Set flag to show that an error occured
bra MoveAhead ;go back to main program to check next
Include "C:\Routines" ;Routines for line input and output
END